home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Gold Medal Software 2
/
Gold Medal Software Volume 2 (Gold Medal) (1994).iso
/
prog
/
asm_n_z.arj
/
SDDOS.ASM
< prev
next >
Wrap
Assembly Source File
|
1988-01-13
|
62KB
|
1,811 lines
CODE SEGMENT
Org 0100
Main:
Jmp Install
;---------------------------------------------------------------------------;
; ;
; Data Areas, Constants, Etc. ;
; ;
;---------------------------------------------------------------------------;
Version Db CR,'Switch Directory - DOS 1.0',CR,LF
Copyright Db 'Copyright (c) 1987, 1988 by Stephen M. Falatko',CR,LF
FakeEOF Db 26
Errlvl Db 0 ;DOS return code
;
; These are flags set by the command line processing
;
;
RootFlag Db 0 ; signal indicating default to root (0)
CDFlag Db 0 ; signal of specific path (1)
OneDeepFlag Db 0 ; search only current dir (1)
;
; This flag is set to indicate that a subdirectory has been found (ie if its
; 0 at the end then we did not find the subdirectory)
;
Done_Flag Db 0 ; found subdir during search
;
; If this flag is set then help is available if ? is entered on the
; command line
;
HelpFlag Db 1
;
; If this flag is set then we can use the internal stack feature
;
StackFlag Db 1
StackAddress Dw ProgramEndH
;
; The Stack_Pointer points to the internal stack path. This is initialized
; to 0 and changes depending on user input.
;
Stack_Pointer Db 0
InternalStackMsg Db CR,LF,'Internal Stack:',CR,LF,CR,LF,Stopper
Numbers Db ' 0 - ',0
Db ' 1 - ',0
Db ' 2 - ',0
Db ' 3 - ',0
Db ' 4 - ',0
Db ' 5 - ',0
Db ' 6 - ',0
Db ' 7 - ',0
Db ' 8 - ',0
Db ' 9 - ',0
CR_LF Db CR,LF,Stopper
;
; These variables hold the systems Ctrl-Break address so we can restore
; it when we exit
;
CtrlBrkOff Dw 0
CtrlBrkSeg Dw 0
;
; Here we will store the desired subdirectory (and drive if selected)
; as well as the original path and drive
;
Sub_Dir Db 63 Dup (0) ; The sub dir we want to change to
ScratchDirStart Db 'x:\' ; This is a scratch area for the
ScratchDir Db 63 Dup (0) ; GetDir function
OD LABEL Word
OrigDr Db 'x:' ; Original drive
OrigDir Db '\',63 Dup (0) ; and path
RootDir Db 'x:\',0 ; To get vol label
Count Dw 0 ; Number of args on command line
;
; These variables are used by the search routine
;
DtaPointer Dw DtaAreaBegin ; Pointer to our DTA area
Direction Db 0 ; Flag to indicate search subdirs
; of the current dir or not
BackOneDir Db '..',0 ; Asciiz 'filename' to backup
; one directory
SearchAsciiZ Db '*.*',0 ; Search filename
Old_INT_21 LABEL Dword ; Storage for previous INT 21
INT_21Off Dw ?
INT_21Seg Dw ?
FirstTime? Db 1 ; flag to signal first pass
; through INT 21 handler
Command_Addr Dw ? ; segment address of command.com
;
; We want to save the callers DS:DX in the INT 21 handler
;
Callers_DS Dw ? ; caller's data segment
Callers_DX Dw ? ; caller's dx register
CReturn Db 0D
CR_LFString Db 0D,0A,'$'
;
; Command is the string that we look for at the DOS prompt. It must
; be 8 characters long with the empty spaces blanks.
;
Command Db 'SD '
;
; Error messages
;
NoHelp Db CR,LF,'ERROR - Installed without help',CR,LF,Stopper
NoStack Db CR,LF,'ERROR - Installed without Stack feature',CR,LF,Stopper
ErrorMsgs Db CR,LF,'Illegal drive specifier - must be A to z',CR,LF,Stopper
Db CR,LF,'Maximum of 64 characters on command line',CR,LF,Stopper
Db CR,LF,'Illegal character on command line ',CR,LF,Stopper
Db CR,LF,'Currently in root directory ',CR,LF,Stopper
Db CR,LF,'Command line contains an invalid path ',CR,LF,Stopper
Db CR,LF,'Subdirectory Not Found ',CR,LF,Stopper
Db CR,LF,'Selected stack entry is empty ',CR,LF,Stopper
New_INT_21:
PUSH ES,DS,BP,SI,DI,AX,BX,CX,DX
;
; Is this a request for buffered input? If not go to next INT 21.
;
CMP AH,0A ; Function 0A (hex) ?
IF NE JMP Exit_INT_21 ; If not then let's leave ....
;
; Let's get the length of the original caller's buffer DS:DX points
; to caller's buffer with the first byte holding the maximum length.
;
MOV BX,DX
DS MOV CL,B [BX]
;
; Save DS and DX of calling program and make DS equal to CS
;
PUSH DS ; Store caller's DS
MOV DS,CS ; Change DS to CS
POP Callers_DS ; Pop caller's DS to Old_DS
PUSH DX ; Store caller's DX
POP Callers_DX
;
; We will use our command line for a buffer so copy the max length of the
; callers buffer to the first position of the new buffer
;
MOV BX,080 ; Point BX to the PSP command line
MOV B [BX],CL ; Store the buffer length in the
; first position
;
; Point the BP to the SP
;
MOV BP,SP
;
; Now, if it's the first time through here then COMMAND.COM is calling and we
; save the segment address off the stack. By doing this we can later
; verify if a caller is COMMAND.COM or not.
;
TEST FirstTime? ; If not the first time go on
JZ Not_First_Time
SS MOV BX,W [BP+4] ; Get COMMAND.COM's segment address
MOV Command_Addr,BX ; Save it
MOV FirstTime?,0 ; Clear flag
JMP Intercept
;
; If this is not the first time through then we want to see if the caller
; is COMMAND.COM or not.
;
Not_First_Time:
SS MOV BX,W [BP+4] ; Get caller's segment address
CMP BX,Command_Addr ; Compare it with COMMAND.COM'S
IF NE JMP Exit_INT_21 ; If its not the same go to next INT 21
;
; Now we know that the caller is DOS so let's get the user input into our
; own temporary buffer so we can check it against our commands.
;
; We begin by setting up a DOS call for buffered input.
;
Intercept:
MOV DX,080 ; Point DS:DX to our PSP
MOV AH,0A ; DOS function call 0A hex
PUSHF ; Simulate DOS interrupt
CALL Old_INT_21
;
; We have performed the caller's INT 21 call, now we must see if the
; entered command is one of ours or whether we must pass it on to COMMAND.COM
;
PUSHF ; First save the flags
CLD ; and clear the direction flag
;
; To simplify our comparison we will use DOS function 29 hex, parse filename,
; to strip leading blanks and capitalize the input string. We will store the
; result in the PSP FCB #1 location
;
MOV ES,CS ; Make ES equal CS
MOV SI,082 ; The source string starts in the PSP
MOV DI,05C ; Destination is in the PSP
MOV AX,02901 ; Parse filename call, strip leading
; seperators (blanks etc.)
PUSHF ; Simulate DOS interrupt
CALL Old_INT_21
;
; Now, we have a copy of the entered command capitalized and stripped of
; leading blanks at offset 5D in the PSP. The question is, is the command
; one of ours ?
;
PUSH SI
MOV SI,OFFSET Command ; SI points to our command
MOV DI,05D ; DI points to what has been typed in
MOV CX,8 ; Check 8 characters
REPE CMPSB
JCXZ Its_Ours ; If CX is zero all characters matched
JMP Send_It_to_CC ; If not then we need to put command
; in COMMAND.COM's buffer.
;
; We have found our command in the buffer so we process the request.
; First we'll output a carriage return - line feed sequence to the
; monitor.
;
Its_Ours:
MOV DX,OFFSET CR_LFString
MOV AH,09 ; print CRLF sequence
PUSHF
CALL Old_INT_21
;
; Now we want to get back SI, which points to the first character after
; SD on the command line. Then we can call the main processor
;
POP SI
CALL Main_Process
;
; We're done so we point BP to a CR, clean the stack and go on.
;
MOV BP,OFFSET CReturn ; Point BP to a carriage return
; character
POPF
JMP SITC
;
; Now its time to send deal with COMMAND.COM's buffer. If we found one of
; our commands then BP points to a CR. Otherwise BP will point to the user's
; command that is in our PSP at OFFSET 082 (hex).
;
Send_It_to_CC:
POP SI
POPF ; Get flags off the stack
MOV BP,082 ; Point BP to the entered data (in
; our PSP)
SITC: ; Entry point if we found one of our
; commands
PUSH Callers_DS ; Make ES equal to COMMAND.COM's DS
POP ES ; that we saved
MOV DI,Callers_DX ; Point DI to COMMAND.COM's DX
ADD DI,2 ; Move past the length specifiers
MOV SI,BP ; Point SI to BP
MOV AL,0 ; Initialize counter for string length
;
; Now that all the bookkeeping is done we can move the string to DOS's
; buffer.
;
Move:
MOVSB ; Move byte
CMP B [SI-1],0D ; Last character moved a CR ?
JE Finished_Move ; If so we are done
INC AL ; Otherwise increment counter
JMP Short Move ; and continue
;
; Our last step is to store the length of the string in COMMAND.COM's
; buffer
;
Finished_Move:
MOV DI,Callers_DX ; Point DI to COMMAND.COM's DX
INC DI ; Increment it
MOV B [DI],AL ; Store actual string length
;
; Now we can leave ....
;
POP DX,CX,BX,AX,DI,SI,BP,DS,ES
IRET
Exit_INT_21:
POP DX,CX,BX,AX,DI,SI,BP,DS,ES
CS JMP Old_INT_21
;---------------------------------------------------------------------------;
; Main_Process ;
; ;
; Main_Process performs all the searching and switching that is the ;
; heart of SDDOS ;
; ;
;---------------------------------------------------------------------------;
Main_Process:
CALL SetUP ; Save current drive and path, reset drive
;
; We begin by determining if there are any command line arguments.
; We look in the PSP for the command line count.
;
CALL StripBlanks ; Strip any leading blanks
CMP B [SI],CR ; Next character a carriage return ?
JE No_Parameters
MOV CX,SI ; Get the number of characters on the
SUB CX,082 ; command line (from the PSP)
MOV AL,B [081] ; Any characters left on command line ?
SUB AX,CX
CMP AX,64 ; more than 64 characters not allowed
JA Got_Parameters
MOV Errlvl,2
JMP Error_Found
;
; If we find nothing then we show the current path and leave
;
No_Parameters:
CALL ShowPath ; set root dir and leave
JMP Exit
;
; We have found some parameters so we processes them.
;
Got_Parameters:
CALL CommandLine
;
; If the carry flag is set when we exit CommandLine we were unsuccessful
;
JC Error_Found
;
; If Done_Flag is set then we were successful, we're finished and we can leave
;
TEST Done_Flag
IF NZ JMP Exit
;
; If we return from CommandLine with CDFlag set that indicates that a
; specific path has been selected and we switch to that specified path.
; Otherwise we search for the desired subdirectory
;
TEST CDFlag
JZ Look_For_The_Subdir
CALL SetPath
;
; If the carry flag is set upon return from SetPath the path does not
; exist and we display the not found message and return to the starting point
; otherwise we're through and we can leave
;
IF NC JMP SHORT Exit
MOV Errlvl,5 ; signal error type (invalid path)
JMP SHORT Error_Found
;
; Now if CDFlag was not set we must search for the subdir. We will begin by
; searching the current directory (like the CD command) and then, if required,
; we'll search the rest of the disk.
;
Look_For_The_Subdir:
MOV OneDeepFlag,1 ; search current level
CALL GetDir ; Read the directory
;
; Now, we reset OneDeepFlag just in case and see if we were successfull
;
MOV OneDeepFlag,0 ; reset OneDeepFlag
TEST Done_Flag ; did we find it?
JNZ Exit ; found it so leave
;
; If we were not successful searching the current directory then we search
; more of the disk. (if rootflag is set then we search the whole disk,
; otherwise we search only the subordinate directories.
;
TEST RootFlag ; default to the root directory?
IF Z CALL No_Arg ; if not equal set to root for search
CALL GetDir ; Read the directory
;
; If Done_Flag is set then we have been successful, otherwise we did not
; find the desired subdirectory.
;
TEST Done_Flag
JNZ Exit
MOV Errlvl,6 ; signal error type (subdir not found)
JMP SHORT Error_Found
;
; If we make it here we have not found the subdirectory so we tell the user
; and return them to the starting drive:subdirectory.
;
Error_Found:
;
; We begin by sending a message to the user
;
CALL Error_Message
;
; Now we reset the drive if it has been changed.
;
SUB DX,DX ; clear DX
MOV DL,OrigDr ; get original drive
CMP DL,RootDir ; compare with current drive
;
; If the selected directory does not match the original directory reset
;
JE Same_Drive
SUB DL,'A' ; change DL from ascii
Set_Drive ; Macro...
;
; Now we reset to our original path and leave
;
Same_Drive:
Change_Dir OrigDr ; Set path to original path (Macro...)
Exit:
MOV RootFlag,0 ; reset flags for next time
MOV CDFlag,0
MOV OneDeepFlag,0
MOV Done_Flag,0
MOV Errlvl,0
MOV DtaPointer,offset DtaAreaBegin ; reset pointer to our DTA
MOV DI,[DtaPointer]
MOV AX,0
MOV CX,43
Dta_Clear:
STOSW
LOOP Dta_Clear
;
; During the Setup procedure we took over the Ctrl-Break address
; so now we restore it.
;
MOV DX,CtrlBrkOff ; Ctrl-Break offset
MOV DS,CtrlBrkSeg ; Ctrl-Break segment
MOV AX,02523 ; set interrupt vector
MOV DS,CS
PUSHF
CALL Old_INT_21
RET ; yes, exit with far return
;---------------------------------------------------------------------------;
; Error_Message ;
; ;
; Error_Message takes the error in errlvl and displays the appropriate ;
; message ;
; ;
;---------------------------------------------------------------------------;
Error_Message:
XOR AX,AX ; clear AX
MOV DX,OFFSET ErrorMsgs ; point to the beginning of the error msgs
MOV AL,Errlvl ; which error?
DEC AX ; decrement for position
MOV CX,45 ; characters per message
MUL CL ; times error type-1
ADD DX,AX ; point to it
CALL PrintS
RET
;---------------------------------------------------------------------------;
; No_Arg ;
; ;
; No_Arg resets the current path to the root directory. ;
; ;
;---------------------------------------------------------------------------;
No_Arg:
; If no argument then set current
Change_Dir RootDir ; path to root directory
RET
;---------------------------------------------------------------------------;
; SetUp ;
; ;
; SetUp initializes some variables and resets the disk drives ;
; ;
;---------------------------------------------------------------------------;
SetUp:
PUSH DX,SI,ES
;
; We begin with a disk reset
;
MOV AH,0D ; Reset diskettes
PUSHF
CALL Old_INT_21
;
; Now we call DOS for the current disk drive and store the information
; as an ascii drive specifier in several variables for future use
;
Current_Disk ; Get current disk (Macro...)
ADD AL,'A'
MOV OrigDr,AL ; Save original drive letter
MOV RootDir,AL ;
MOV ScratchDirStart,AL
;
; We also want to store our current path so we can return if necessary
MOV DL,OrigDr ; put original drive in DL
SUB DL,'@' ; convert from ascii character
MOV SI,OFFSET OrigDir + 1 ; the original drive
Get_Path ; Macro...
;
; Our last task is to point the Ctrl+Break vector to our Not_Found code
; so the user is left where they began if using Ctrl+Break. But first we
; store the current Ctrl-Brk vector so we can restore it when we leave
;
MOV AX,03523 ; call DOS for Ctrl-Break location
PUSHF
CALL Old_INT_21
MOV CtrlBrkSeg,ES
MOV CtrlBrkOff,BX
;
; Now let's set up our Ctrl-Brk.
;
MOV AX,02523 ; set Ctrl+Break vector to point
MOV DX,OFFSET CtrlBrk ; to our not found. This way a Ctrl+Brk
; will leave us in the place we started
PUSHF
CALL Old_INT_21
POP ES,SI,DX
RET
;---------------------------------------------------------------------------;
; CommandLine ;
; ;
; CommandLine parses the command line, looking for switches and sub- ;
; dir names ;
; ;
;---------------------------------------------------------------------------;
CommandLine:
;
; We begin by setting DI
;
MOV DI,OFFSET Sub_dir ; point DI to our internal buffer for
; the desired sub directory name
;
; We check for two switches, the internal stack switch and the enqueue switch.
; If we find either in the first position we don't check the command line
; for a drive specifier.
;
CMP B [SI],'"'
JE Parse_Command_Line
CMP B [SI],'['
JE Parse_Command_Line
CALL Do_Drive
CMP Errlvl,1
IF E JMP ExitCL
CALL StripBlanks
CMP B [SI],CR
JNE Parse_Command_Line
MOV Done_Flag,1
JMP ExitCL
;
; We've now found a drive if it has been specified and we're ready
; to look at the rest of the command line
;
Parse_Command_Line:
LODSB ; get character from command line and
; put it in al
CMP AL,CR ; is it a carriage return ?
IF E JMP We_Are_Finished ; if so we're at the end so jump on
;
; If we find a '.' character we must check for '..' which CD uses
; to go back one level
;
Back_One?:
CMP AL,'.'
JNE Display_Help?
;
; We found one '.' but are there two?
;
CMP W [SI-1],'..' ; two periods?
JE Go_Back_One ; if so back one dir.
;
; If there are not two periods, we may have an extension on the subdir
; name. We check to see if the period is the first character and if it is
; we assume an error, otherwise we process it and go on.
;
CMP DI,OFFSET Sub_Dir ; is it the first character ?
IF NE JMP Process_Character ; if not then process it
STC ; otherwize - ERROR!
MOV Errlvl,3 ; signal error type (illegal character)
JMP ExitCL
Go_Back_One:
Change_Dir BackOneDir ; change back one
JNC Go_Back_One_Worked
MOV Errlvl,4 ; signal error type (in root)
JMP ExitCL ; leave
Go_Back_One_Worked:
MOV Done_Flag,1 ; else set done_flag and leave
JMP ExitCL ; do a not so nice jump to exit
;
; If the help character (?) is the first character on the command line
; then we display the help message and leave
;
Display_Help?:
CMP AL,'?' ; help character?
JNE Go_Home?
CMP DI,OFFSET Sub_Dir ; is it the first character ?
JNE Do_Internal_Stack
;
; Now that we have found the help character is help available?
;
TEST HelpFlag ; help info loaded ?
JNZ Show_Help ; yes so display it
;
; Help not available, display message.
;
MOV DX,OFFSET NoHelp ; display error message and leave
CALL PrintS
MOV Done_Flag,1
JMP ExitCL
Show_Help:
MOV DX,OFFSET Help ; yes, let's display the help screen and
CALL PrintS ; then leave
MOV Done_Flag,1
JMP ExitCL
;
; Set the path to the one indicated in Stack_Pointer ?
;
Go_Home?:
CMP AL,'@' ; jump 'home' ?
JNE Do_Internal_Stack
CMP B [SI],CR ; next character a carriage return ?
IF NE JMP Kill? ; if not assume a valid @ in path name
MOV AL,Stack_Pointer ; get pointer to current location
PUSH AX ; save stack position
CALL StackBufferPos ; get offset into stack buffer
CMP B [SI],0 ; empty stack position ?
IF NE JMP MoveToPath ; if so error
POP AX ; clear stack
JMP No_Internal_Path ; leave
;
; If we find a @" on the command line then we want to kill ourselves.
;
Kill?:
CMP B [SI],'"'
IF NE JMP Process_Character ; if not assume a valid @ in path name
;
; Time to kill ourselves .....
;
PUSH DS
MOV AX,02521 ; Revector INT 21 to
MOV DX,INT_21Off ; the previous INT 21
MOV DS,INT_21Seg
PUSHF
CS CALL Old_INT_21
POP DS
MOV AH,049 ; And free up our memory. (remember
MOV ES,CS ; that the environment was already
; deallocated during installation)
PUSHF
CALL Old_INT_21
MOV Done_Flag,1
JMP ExitCL
;
; If we find the '"' switch we are to process the internal 'stack'. There
; are several possible options: 1) + go to next highest stack path (wraps)
; 2) - go to the next lowest stack path (wraps) 3) (Number) go to path
; number.. 4) (Number)= (several options) change internal stack
;
; We first check to see if we are enqueued to CED (or PCED). If we are
; not then we go on.
;
Do_Internal_Stack:
CMP AL,'"' ; Stack command switch?
IF NE JMP Search_Below?
CMP DI,OFFSET Sub_Dir ; is it the first character ?
IF NE JMP ErrorIS
TEST StackFlag ; stack memory available?
JNZ Do_Stack ; yes
;
; Its not available, display error message.
;
MOV DX,OFFSET NoStack ; display error message and leave
CALL PrintS
MOV Done_Flag,1
JMP ExitCL
;
; We have a valid '"' character so we begin by incrementing DI to point
; to the next command line character and checking to see if it is a '+'
;
Do_Stack:
CALL StripBlanks ; remove leading blanks
CMP B [SI],'+' ; Jump to next highest dir ?
JNE Jump_Back?
MOV AL,Stack_Pointer ; get pointer to current location
;
; Now, let's jump to the next highest OCCUPIED (no 0 in first position)
; stack position
;
J1:
INC AL ; increment stack pointer
CMP AL,0A ; over 9 ?
IF E MOV AL,0 ; if so wrap to 0
CALL StackBufferPos ; get offset into stack buffer
CMP B [SI],0 ; empty stack position ?
JE J1 ; yes - try another
PUSH AX ; save stack position
JMP MoveToPath ; move to the new path
;
; Now, let's jump to the next lowest OCCUPIED (no 0 in first position)
; stack position
;
Jump_Back?:
CMP B [SI],'-' ; jump to next lowest dir ?
JNE Jump_To_It?
MOV AL,Stack_Pointer ; get pointer to current location
J2:
DEC AL ; decrement stack pointer
CMP AL,0FFFF ; less than 0 ?
IF E MOV AL,9 ; if so wrap to 9
CALL StackBufferPos ; get offset into stack buffer
CMP B [SI],0 ; empty stack position ?
JE J2 ; yes - try another
PUSH AX ; save stack position
JMP MoveToPath ; move to the new path
;
; Are we manipulating a specific stack entry ? If we find a 0 to 9 we are.
;
Jump_To_It?:
CMP B [SI],'0' ; Below 0 ? If so error
IF B JMP ErrorIS
CMP B [SI],'9' ; Above 9 ? If so might be show stack
JA Show_Stack?
CMP B [SI+1],'=' ; next char = ? If so modifing entry
JE Stack_Entry
JMP Set_Internal_Path ; otherwise move to that path
;
; Display the internal stack if s or S selected.
;
Show_Stack?:
CMP B [SI],'S' ; S or s entered ? If not error
IF NE CMP B [SI],'s'
IF NE JMP ErrorIS
;
; Display header and setup variables
;
MOV DX,OFFSET InternalStackMsg ; display header
CALL PrintS
MOV DX,StackAddress ; store address of stack buffer
PUSH DX
MOV BX,OFFSET Numbers ; point to numbers (0 -, 1-, etc)
MOV CX,0A ; loop 10 times
;
; This loop will print out the contents of each stack position
;
S1:
MOV DX,BX ; print the 0 -, 1 -
CALL PrintS
POP DX ; get back address to stack
CALL PrintS ; print stack item
ADD DX,64 ; point to next stack item
PUSH DX ; save it
MOV DX,OFFSET CR_LF ; print CR,LF sequence
CALL PrintS
ADD BX,6 ; point to next number (0 -...)
LOOP S1
POP DX ; all done, clean up stack, set flag
MOV Done_Flag,1 ; and leave
JMP ExitCL
Stack_Entry:
SUB AX,AX ; clear AX
MOV AL,B [SI] ; get number from command line
SUB AL,030 ; convert from ascii
PUSH SI ; get offset into stack buffer
CALL StackBufferPos
MOV DI,SI
POP SI
ADD SI,2 ; now point past '='
CMP B [SI+1],':' ; second character drive seperator ?
JE StoreThePath ; If so we can go on
MOV AX,OD ; store drive specifier incase some
MOV W [DI], AX ; stack paths switch the drive
ADD DI,2
CMP B [SI],'\' ; path on command line ?
JE StoreThePath ; if so store it
CMP B [SI],'@' ; get current path switch ?
JE StoreCurrentPath
CMP B [SI],' ' ; blank on command line ?
IF NE JMP ErrorIS ; if so clear entry
MOV B [DI-2],0
MOV Done_Flag,1
JMP ExitCL
;
; If the @ switch is on the command line we store the current path
; in the specified stack position.
;
StoreCurrentPath:
MOV B [DI],'\' ; start by inserting \ in buffer
INC DI
MOV DL,0 ; default drive
MOV SI,DI
Get_Path ; call DOS for the path
MOV Done_Flag,1 ; leave
JMP ExitCL
StoreThePath:
LODSB ; get character from command line and
; put it in al
CMP AL,CR
JE AllStored
CMP AL,'a' ; lowercase letter?
IF AE XOR AL,020 ; if so make upper case
;
; Now we have an upper case character let's store it in our buffer and
; go get the next
;
STOSB
JMP SHORT StoreThePath
AllStored:
MOV B [DI],0 ; a zero at the end of the path
MOV Done_Flag,1 ; to create an asciiz string
JMP ExitCL
;
; Set_Internal_Path sets the path to that specified in the desired internal
; buffer. If the path is empty (first position 0) an error is issued
;
Set_Internal_Path:
SUB AX,AX ; get number from command line and
MOV AL,B [SI] ; convert from ascii
SUB AL,030
PUSH AX ; save value
CALL StackBufferPos ; get offset into stack buffer
CMP B [SI],0 ; Ascii null (no path set) ?
JNE MoveToPath ; if so error
POP AX ; clear stack
JMP SHORT No_Internal_Path ; leave
;
; We can now find the path and move there. (NOTE: the + and - functions
; come here to set the path.
;
MoveToPath:
CALL Do_Drive ; scan path for a drive identifier and
; set drive
CMP B [SI],0 ; anything more in path ?
JE ExitSIP ; no, so exit
MOV DX,SI ; change path to that specified
MOV AH,ChangeDir
PUSHF
CALL Old_INT_21
JNC ExitSIP ; if there is no carry (error) leave
POP AX ; clean up stack
JMP BadPath ; leave
ExitSIP:
POP AX ; get back stackpointer
MOV Stack_Pointer,AL
MOV Done_Flag,1 ; signal done and leave
JMP ExitCL
BadPath:
STC
MOV Errlvl,5 ; signal error type (invalid path)
JMP ExitCL
ErrorIS:
STC
MOV B [DI-2],0
MOV Errlvl,3 ; signal error type (illegal character)
JMP ExitCL
No_Internal_Path:
STC
MOV Errlvl,7 ; signal error type (Stack entry empty)
JMP ExitCL
;
; The / switch indicates that we are only to search for subdirectories of
; the current directory. (This was changed in version 3.0 of SD)
;
Search_Below?:
CMP AL,'/' ;search below (/) switch ?
IF NE JMP Path_Specified?
;
; If we find this character we want to know if its the first character of the
; command line or not.
;
CMP DI,OFFSET Sub_Dir ; have we stored any characters yet?
JNE SB_Not_First_Char
;
; If it is the first we set a flag to keep us from defaulting to the
; root directory before we search
;
MOV RootFlag,1 ; signal to search below, not reset to
JMP SHORT Parse_Command_Line ; root
;
; Now, if its not the first character on the command line we need to
; do some fancy footwork. First we need to see if a specific path
; has previously been signaled.
;
SB_Not_First_Char:
TEST CDFlag ; have we already seen a specific
; path on the command line?
JZ SB_No_Path_Yet ; no so go on
;
; A specific path has been previously selected so we make this path an
; asciiz string and switch to it. Upon completion we reset DI to the
; begining of our command line buffer and clear the specific subdir flag.
;
MOV B [DI],0 ; make current path asciiz string
CALL SetPath ; change to the already specified path
;
; If the carry flag is set there was an error in the path (usually it didn't
; exist)
;
JNC SB_Not_First_Char_Done ; if the subdir doesn't exist leave
MOV Errlvl,5 ; signal error type (invalid path)
JMP ExitCL ; leave
;
; If the path existed then we reset DI to the beginning of our buffer,
; reset CDFlag and set RootFlag.
;
SB_Not_First_Char_Done:
MOV DI,OFFSET Sub_Dir ; reset DI
MOV CDFlag,0 ; clear specific subdir flag
MOV RootFlag,1 ; search below, don't default to root
JMP SHORT Parse_Command_Line ; go get next char
;
; It hasn't so this means that we search the disk for the subdir specified
; up till now (on the command line). To do this we must make the name an
; asciiz string, search for it then specify that we don't want to default
; to the root directory before out next search. DI must also be reset.
; In doing the search we imitate the CD command by first searching the current
; level and then enhance it by searching the whole disk (if RootFlag set,
; otherwise search only below current dir)
;
SB_No_Path_Yet:
MOV B [DI],0 ; make current path asciiz string
MOV Count,DI ; how many characters stored?
SUB Count,OFFSET Sub_Dir ; we need to set this for GetDir
;
; Set OneDeepFlag so we only check current directory
;
MOV OneDeepFlag,1 ; start by searching current level
CALL GetDir ; search for path already specified
;
; Reset OneDeepFlag, check to see if we are done and if so move on
;
MOV OneDeepFlag,0 ; reset the OneDeepFlag
TEST Done_Flag ; see if we were successful
JNZ Search_A_Success ; if so leave
;
; ..otherwise re-search. We reset to the root directory if RootFlag is set
;
TEST RootFlag ; searching only below?
IF Z CALL No_Arg ; set to root for search
MOV Count,DI ; how many characters stored?
SUB Count,OFFSET Sub_Dir ; we need to set this for GetDir
CALL GetDir ; search for path already specified
;
; If Done_Flag is set then we have found our directory, otherwise we set
; the carry flag and leave
;
TEST Done_Flag ; see if we were successful
JZ Search_A_Success ; if not leave
STC
MOV Errlvl,6 ; signal error type (subdir not found)
JMP ExitCL
;
; We found the subdir, now reset Done_Flag for future use as well as DI
;
Search_A_Success:
MOV Done_Flag,0 ; reset Done_Flag incase of future searches
MOV RootFlag,1 ; search below, don't default to root
MOV DI,OFFSET Sub_Dir ; reset DI
JMP Short Parse_Command_Line
;
; The \ switch indicates a specific path is specified. (i.e. no searching
; just switch to this path.
;
Path_Specified?:
CMP AL,'\' ; Path seperator/indicator (\) ?
IF NE JMP Process_Character
;
; If we find this flag we want to know if its the first character of the
; command line or not.
;
CMP DI,OFFSET Sub_Dir ; still pointing to beginning?
JNE PS_Not_First_Char
;
; If it is the first we set a flag to indicate a specific subdir has been
; selected.
;
Change_Dir RootDir ; make sure we are at the root dir
MOV CDFlag,1 ; set flag to select specific subdir
;
; Strip any leading blanks.....
;
CALL StripBlanks
;
; If all that's left is a carriage return we are done, otherwise get the next.
;
CMP B [SI],CR
IF NE JMP Short Parse_Command_Line
MOV Done_Flag,1
JMP ExitCL
;
; If its not the first character we check to see if another one has already
; been found.
;
PS_Not_First_Char:
TEST CDFlag ; already set to look for path?
JNZ Already_Reading_Path ; yes so go on
;
; None has been found yet so we make the current string (in the buffer)
; an asciiz string and go search for the subdir it specifies. After
; the search we reset DI, Done_Flag and CDFlag.
;
MOV B [DI],0 ; make string asciiz
;
; Set the character count and a flag to search the current level
;
MOV Count,DI ; how many characters stored?
SUB Count,OFFSET Sub_Dir ; we need to set this for GetDir
MOV OneDeepFlag,1 ; start by searching current level
CALL GetDir ; search for path already specified
;
; Reset the OneDeepFlag and see if we found our subdir
;
MOV OneDeepFlag,0 ; reset the OneDeepFlag
TEST Done_Flag ; see if we were successful
JNZ PS_Search_A_Success ; if not leave
;
; If we didn't find the dir we check to see if we reset to the root and
; continue on with the search.
;
TEST RootFlag ; reseting to root ?
IF Z CALL No_Arg ; set to root for search if flag not set
MOV Count,DI ; how many characters stored?
SUB Count,OFFSET Sub_Dir ; we need to set this for GetDir
CALL GetDir ; search for specified path
;
; We have searched the desired part of the drive, now did we find anything?
;
TEST Done_Flag ; see if we were successful
;
; If we did we reset the flags and continue on, otherwise leave.
;
JNZ PS_Search_A_Success ; if not leave
STC ; set carry flag to signal error
MOV Errlvl,6 ; signal error type (subdir not found)
JMP Short ExitCL
PS_Search_A_Success:
MOV Done_Flag,0 ; reset Done_Flag incase of future searches
MOV DI,OFFSET Sub_Dir ; reset DI
MOV CDFlag,1 ; indicate specific path
JMP Short Parse_Command_Line
;
; If we have already seen a path seperator we continue building the
; desired path in our buffer.
;
Already_Reading_Path:
STOSB
JMP Short Parse_Command_Line ; and get next char
;
; Now we make sure the character is upper case because DOS doesn't like
; lower case. There is potential for error here because these checks will
; pass some invalid characters (for DOS filenames). The result is some
; delay before an error is found.
;
Process_Character:
CMP AL,'!' ; compare with !
IF B JMP Parse_Command_Line ; get next char if smaller
CMP AL,'z' ; compare with z
IF A JMP Parse_Command_Line ; get next char if bigger
CMP AL,'a' ; lowercase letter?
JB Store_The_Character ; nope so go on
XOR AL,020 ; make upper case
;
; Now we have an upper case character let's store it in our buffer and
; go get the next
;
Store_The_Character:
STOSb
JMP Short Parse_Command_Line
;
; When we get here we're done with the command line and we must make
; sure that we have an asciiz name in our buffer.
;
We_Are_Finished:
MOV Count,DI ; how many characters stored?
SUB Count,OFFSET Sub_Dir
;
; If count is zero we have not found anything on the command line so let's
; reset to the root directory and leave
;
CMP Count,0
JNE Something_In_Buffer
;
; Show the path
;
CALL ShowPath ; display the path
MOV Done_Flag,1 ; signal done
JMP SHORT ExitCL ; leave
;
; We found something so let's make sure its an asciiz string
;
Something_In_Buffer:
MOV AL,0
STOSB
JMP SHORT ExitCL
ExitCL:
RET
;---------------------------------------------------------------------------;
; Do_Drive ;
; ;
; The procedure Do_Drive scans for a drive specifier. If one is found, ;
; and it is different from the default drive, the drive is changed. ;
; ;
;---------------------------------------------------------------------------;
Do_Drive:
PUSH DI
MOV DI,SI
MOV AL,':' ; we'll look for a ':'
REPNE SCASB
JNE ExitDD ; if we did not find a ':' then leave
;
; If we did find a drive letter then we set SI to point to the char after ':'
;
MOV SI,DI ; now, point SI to the character following
; the ':' character
;
; We now point DI to the drive letter and put it in AL
;
MOV AL,B [DI-2] ; save the drive specifier in al - again
; the segment override is needed for CED)
;
; We must check the drive letter to see that it is a letter and then make sure
; it is capitalized
;
CMP AL,'A' ; compare with A
IF B JMP DriveError ; if smaller then it is an erroneous drive
CMP AL,'z' ; compare with z
IF A JMP DriveError ; if larger then it is an erroneous drive
CMP AL,'a' ; lowercase letter?
JB New_Drive? ; no its upper case so lets go on
XOR AL,020 ; make upper case
;
; Now we have an uppercase drive letter we first check to see that it is
; different from the original drive if its not we go on.
;
New_Drive?:
CMP OrigDr,AL
JE ExitDD
;
; We have a different drive letter so lets store it and the change drives
;
MOV RootDir,AL ; save new drive specifier
MOV ScratchDirStart,AL
;
; After saving we call DOS and change the drive to the desired one
;
SUB DX,DX ; clear dx
MOV DL,AL ; must change drive to number, not ascii
SUB DL,'A'
Set_Drive ; Macro....
JMP ExitDD
;
; If an illegal drive was specified on the command line we come here and
; display and error message. The Done_Flag is then set and we return to
; the main program.
;
DriveError: ; we come here if the drive specifier
; is not in A to z
POP DI
MOV Errlvl,1
STC
ExitDD:
POP DI
RET
;---------------------------------------------------------------------------;
; StripBlanks ;
; ;
; StripBlanks, of all things, strips leading blanks from the command ;
; line. ;
; ;
;---------------------------------------------------------------------------;
StripBlanks:
CMP B [SI],' '
IF NE RET
INC SI
JMP SHORT StripBlanks
;---------------------------------------------------------------------------;
; StackBufferPos ;
; ;
; StackBufferPos determines the offset into the stack buffer for a ;
; specified stack item. The number of the item is in al. ;
; ;
;---------------------------------------------------------------------------;
StackBufferPos:
PUSH AX
SUB AH,AH
MOV SI,StackAddress
MOV CX,64
MUL CL
ADD SI,AX
POP AX
RET
;---------------------------------------------------------------------------;
; GetDir ;
; ;
; GetDir searches for the desired subdirectory. The extent of the ;
; search can be modified by command line switches ;
; ;
; Based on WHISK by Charles Wooster ;
;---------------------------------------------------------------------------;
GetDir:
PUSH SI,DI
MOV Done_Flag,0
; Find first or next subdirectory level
; -------------------------------------
NextLevel:
MOV DX,[DTAPointer] ; Next nested DTA
MOV AH,1Ah ; For DOS call to set DTA
INT 21h ; Do it
CMP [Direction],0 ; Check if we're nesting
JNZ FindNextFile ; If not, we're continuing
MOV DX,OFFSET SearchAsciiZ ; We search for *.*
MOV CX,12h ; Subdirectory attribute + hidden attrib
MOV AH,4Eh ; Find first file
INT 21h ; by calling DOS
JMP Short TestMatch ; Hop around next section
FindNextFile:
MOV AH,4Fh ; Find next file
INT 21h ; by calling DOS
TestMatch:
JC NoMoreFiles ; If CY flag, at end of rope
MOV BX,[DTAPointer] ; Our find stuff is here
TEST B [BX + 21],10h ; Test if directory attribute
JZ FindNextFile ; If not, continue search
ADD BX,30 ; Now points to directory name
CMP Byte Ptr [BX],'.' ; Ignore "." and ".." entries
JZ FindNextFile ; by continuing the search
TEST OneDeepFlag ; looking only at this level?
JNZ Compare
PUSH BX ; save pointer to subdir name
MOV DX,BX ; Now DX points to found dir
MOV AH,3Bh ; Set up DOS function call
INT 21h ; And change directory
POP BX ; get pointer to subdir name back
Compare:
SUB CX,CX
MOV CX,Count
MOV DI, Offset Sub_Dir
LEA SI, BX
REPE CMPSB
JZ Found ; matched up so leave
TEST OneDeepFlag
JZ GoOn
MOV [Direction],-1
JMP SHORT NextLevel
GoOn:
ADD [DtaPointer],43 ; New DTA for new level
MOV [Direction],0 ; I.E., Find first file
JMP NextLevel ; All ready to cycle through
; No More Files Found -- go back to previous level
; ------------------------------------------------
NoMoreFiles:
CMP [DTAPointer],OFFSET DtaAreaBegin ; See if back at start
JZ ExitGD ; If so, that's all, folks
SUB [DTAPointer],43 ; Back one for previous
MOV [Direction],-1 ; I.E., will find next file
MOV DX,OFFSET BackOneDir ; The string ".."
MOV AH,3Bh ; CALL to change directory
INT 21h ; Change directory to father
JMP NextLevel ; And continue the search
Found:
TEST OneDeepFlag
IF Z JMP SHORT F1
MOV DX,BX ; Now DX points to found dir
MOV AH,3Bh ; Set up DOS function call
INT 21h ; And change directory
F1:
MOV Done_Flag,1
ExitGD:
MOV [Direction],0
POP DI,SI
RET
;---------------------------------------------------------------------------;
; SetPath ;
;